home *** CD-ROM | disk | FTP | other *** search
- ;-----------------------------------------------------------------------;
- ; COMLIB.ASM Communication library for C. ;
- ; ;
- ; Pictor, Version 1.51, Copyright (c) 1992-94 SoftCircuits. ;
- ; Redistributed by permission. ;
- ;-----------------------------------------------------------------------;
- % .MODEL memmodel,c
-
- EXTRN atexit:PROC
-
- .DATA
- PUBLIC _PL_comtimeout,_PL_comoverflow
- _PL_comtimeout DW 90 ;Number of 18ths/second before timeout
- _PL_comoverflow DW 0 ;1 if data buffer overflows
-
- BUFSIZ EQU 512 ;Size of serial port data buffer
- buffer DB BUFSIZ DUP (0) ;Serial port data buffer
- buff_head DW OFFSET buffer
- buff_tail DW OFFSET buffer
- buff_count DW 0 ;Number of bytes in buffer
-
- iobase DW 0 ;Base I/O address for serial port
- int_mask DB 0 ;01h SHL IRQn
- int_num DB 0 ;IRQn + 08h
-
- old_handler DD 0 ;Original interrupt handler
- installed_flag DB 0 ;1 = handler is installed
- registered_flag DB 0 ;1 = registered w/atexit
- timer DW 0 ;Used for time-out countdown
-
-
- .CODE
- old1C_handler DD 0 ;Original timer handler (in code seg)
-
- ;-----------------------------------------------------------------------;
- ; This procedure becomes the handler for interrupt-driven ;
- ; communications. ;
- ; ;
- ; Usage: This procedure cannot be called directly from C. ;
- ;-----------------------------------------------------------------------;
- IFDEF ??version ;Turbo Assembler
- int_handler PROC FAR
- ELSE
- int_handler PROC FAR PRIVATE
- ENDIF
- sti
- push ax
- push bx
- push dx
- push ds
- mov ax,@Data ;Set ds = data segment
- mov ds,ax
- mov dx,iobase ;dx = data port address
- in al,dx ;Read most-recently recieved byte
- cmp buff_count,BUFSIZ ;Is data buffer full?
- jnb buffer_full ;Yes, discard character
- mov bx,buff_tail ;Else write character to
- mov [bx],al ; buffer tail
- inc buff_tail ;Bump tail pointer
- cmp buff_tail,OFFSET buffer+BUFSIZ ;End of buffer?
- jb char_stuffed ;No, done
- mov buff_tail,OFFSET buffer ;Else wrap pointer to buffer start
- char_stuffed:
- inc buff_count ;Increment counter
- end_int_handler:
- mov al,20h ;Send end-of-interrupt to 8259
- out 20h,al
- pop ds
- pop dx
- pop bx
- pop ax
- iret
- buffer_full:
- mov _PL_comoverflow,1 ;Set overflow flag
- jmp end_int_handler
- int_handler ENDP
-
- ;-----------------------------------------------------------------------;
- ; Timer interrupt handler. Decrements timer if timer is non-zero and ;
- ; chains to original timer handler. ;
- ; ;
- ; Usage: This procedure cannot be called directly from C. ;
- ;-----------------------------------------------------------------------;
- IFDEF ??version ;Turbo Assembler
- int1C_handler PROC FAR
- ELSE
- int1C_handler PROC FAR PRIVATE
- ENDIF
- sti
- push ax
- push ds
- mov ax,@Data ;Set ds = data segment
- mov ds,ax
- cmp timer,0 ;Are we counting down?
- je end_int1C_handler ;No, get out
- dec timer ;Else decrement timer
- end_int1C_handler:
- pop ds
- pop ax
- cli ;Handler expects interrupts off
- jmp cs:old1C_handler ;Chain to previous handler
- int1C_handler ENDP
-
- PUBLIC comloc
- ;-----------------------------------------------------------------------;
- ; Returns the number of characters waiting in the receive data buffer. ;
- ; ;
- ; Usage: int comloc(void); ;
- ;-----------------------------------------------------------------------;
- comloc PROC
- mov ax,buff_count ;Return number of bytes in
- ret ; buffer in ax
- comloc ENDP
-
- PUBLIC comflush
- ;-----------------------------------------------------------------------;
- ; Clears any characters waiting in the receive data buffer and clears ;
- ; any error conditions. ;
- ; ;
- ; Usage: int comflush(void); ;
- ; Returns: The number of characters flushed from the buffer. ;
- ;-----------------------------------------------------------------------;
- comflush PROC
- mov ax,buff_count ;Return number of character in buffer
- mov buff_head,OFFSET buffer ;Reset buffer pointers
- mov buff_tail,OFFSET buffer
- mov buff_count,0
- mov _PL_comoverflow,0 ;Clear overflow flag
- ret
- comflush ENDP
-
- PUBLIC comclose
- ;-----------------------------------------------------------------------;
- ; Removes communications interrupt handlers and flushes buffers. ;
- ; ;
- ; Usage: int comclose(void); ;
- ; Returns: 0 = success, -1 = error ;
- ;-----------------------------------------------------------------------;
- comclose PROC
- mov ax,-1
- cmp installed_flag,0 ;Are our routines installed?
- je end_comclose ;No, ignore request
- in al,21h ;Read current 8259 mask
- or al,int_mask ;Mask out interrupt
- out 21h,al ;Write it back
- mov ah,25h ;Restore communications handler
- mov al,int_num
- push ds
- lds dx,old_handler
- int 21h
- pop ds
- mov ax,251Ch ;Restore timer handler
- push ds
- lds dx,cs:old1C_handler
- int 21h
- pop ds ;Restore ds
- call comflush ;Flush receive buffer and
- mov timer,0 ; reset timer
- mov installed_flag,0
- sub ax,ax
- end_comclose:
- ret
- comclose ENDP
-
- ;-----------------------------------------------------------------------;
- ; Installs our interrupt vectors and programs the UART. ;
- ; ;
- ; Usage: This procedure cannot be called directly from C. ;
- ;-----------------------------------------------------------------------;
- IFDEF ??version ;Turbo Assembler
- install_handler PROC NEAR
- ELSE
- install_handler PROC NEAR PRIVATE
- ENDIF
- push ax
- push bx
- push dx
- push es
- mov ah,35h ;Save old interrupt vector
- mov al,int_num
- int 21h
- mov WORD PTR old_handler[0],bx
- mov WORD PTR old_handler[2],es
- push ds ;Set new interrupt vector
- mov ah,25h
- mov al,int_num
- push cs
- pop ds
- mov dx,OFFSET int_handler
- int 21h
- pop ds
- mov ax,351Ch ;Get old timer interrupt vector
- int 21h
- mov WORD PTR cs:old1C_handler[0],bx
- mov WORD PTR cs:old1C_handler[2],es
- push ds ;Set new timer interrupt vector
- mov ax,251Ch
- push cs
- pop ds
- mov dx,OFFSET int1C_handler
- int 21h
- pop ds
- mov dx,iobase ;Set modem control register
- add dx,04h ; DTR, RTS and OUT2 bits
- mov al,0Bh
- out dx,al
- mov dx,iobase ;Set interrupt enable register
- add dx,01h ; to interrupt on data received
- mov al,01h
- out dx,al
- mov dl,int_mask ;Program 8259 to enable our IRQ
- not dl
- in al,21h
- and al,dl
- out 21h,al
- pop es
- pop dx
- pop bx
- pop ax
- ret
- install_handler ENDP
-
- PUBLIC comopen
- ;-----------------------------------------------------------------------;
- ; Initializes the communications port and installs our own interrupt ;
- ; handlers. ;
- ; ;
- ; Usage: int comopen(int com_port,int baud_rate,int parity, ;
- ; int data_bits,int stop_bits,int irq_num); ;
- ; Returns: 0 = success, -1 = com port not found ;
- ;-----------------------------------------------------------------------;
- comopen PROC com_port:WORD,baud_rate:WORD,parity:WORD,\
- data_bits:WORD,stop_bits:WORD,irq_num:WORD
- mov ax,-1
- cmp installed_flag,1 ;Are we already installed?
- jne not_installed ;No, continue
- jmp end_comopen ;Else ignore request
- not_installed:
- cmp irq_num,0 ;Was IRQ specified?
- jne irq_ready ;Yes, leave it alone
- mov irq_num,04h ;Else set IRQ4 if COM1 or COM3,
- mov ax,com_port ; IRQ3 if COM2 or COM4
- and ax,0001h
- sub irq_num,ax
- irq_ready:
- mov cx,irq_num ;Calculate and save interrupt
- mov al,01h ; mask value
- shl al,cl
- mov int_mask,al
- add cl,08h ;Calculate and save software
- mov int_num,cl ; interrupt number
- mov ax,0040h ;Get base address for selected
- mov es,ax ; com port from ROM BIOS
- mov bx,com_port
- shl bx,1
- mov dx,es:[bx]
- mov ax,-1 ;Return -1 if port invalid
- cmp dx,0
- je end_comopen
- mov iobase,dx ;Else save port base I/O address
- add dx,03h ;Set bit 7 of line control register
- mov al,80h ; and set baud rate
- out dx,al
- jmp $+2
- mov dx,iobase
- mov ax,baud_rate
- out dx,al ;Write low byte of baud rate divisor
- jmp $+2
- inc dx
- mov al,ah
- out dx,al ;Write high byte of baud rate divisor
- mov dx,iobase ;Initialize line control register
- add dx,03h
- mov ax,data_bits
- or ax,stop_bits
- or ax,parity
- out dx,al
- mov timer,0 ;Reset timer and receive buffer
- call comflush
- call install_handler ;Install our handlers
- mov installed_flag,1 ;Indicate we're installed
- sub ax,ax ;Prepare to return success
- cmp registered_flag,1 ;Have we registered with atexit()?
- je end_comopen ;Yes, done
- mov registered_flag,1
- IF @CodeSize ;Else register comclose with atexit()
- push cs
- ENDIF
- mov ax,OFFSET comclose
- push ax
- call atexit
- IF @CodeSize
- add sp,4
- ELSE
- inc sp
- inc sp
- ENDIF
- cmp ax,0 ;Done if atexit succeeded
- je end_comopen
- call comclose ;Else uninstall ourselves
- mov registered_flag,0
- mov ax,-1 ;Return error
- end_comopen:
- ret
- comopen ENDP
-
- PUBLIC comgetc
- ;-----------------------------------------------------------------------;
- ; Receives one character from the serial port. ;
- ; ;
- ; Usage: int comgetc(char *value); ;
- ; Returns: 0 = success; -1 = error ;
- ;-----------------------------------------------------------------------;
- comgetc PROC value:PTR BYTE
- mov ax,-1 ;Return error if handler is
- cmp installed_flag,0 ; not installed
- je end_comgetc
- mov ax,_PL_comtimeout ;Start timer
- mov timer,ax
- comgetc_wait:
- mov ax,-1 ;Return -1 if we timed-out
- cmp timer,0
- je end_comgetc
- cmp buff_count,0 ;Anything in receive buffer?
- je comgetc_wait ;No, keep waiting
- mov bx,buff_head ;Use bx to access buffer
- mov al,[bx] ;Get next byte in al
- inc buff_head ;Bump pointer
- cmp buff_head,OFFSET buffer+BUFSIZ ;End of buffer?
- jb got_char ;No, done
- mov buff_head,OFFSET buffer ;Else wrap pointer to buffer start
- got_char:
- dec buff_count ;Adjust count
- IF @DataSize
- les bx,value ;Write value to user variable
- mov es:[bx],al
- ELSE
- mov bx,value
- mov [bx],al
- ENDIF
- sub ax,ax ;Return 0
- end_comgetc:
- ret
- comgetc ENDP
-
- PUBLIC computc
- ;-----------------------------------------------------------------------;
- ; Sends one character out the serial port. ;
- ; ;
- ; Usage: int computc(char value); ;
- ; Returns: 0 = success; -1 = error ;
- ;-----------------------------------------------------------------------;
- computc PROC value:BYTE
- mov ax,-1 ;Return error if handler is
- cmp installed_flag,0 ; not installed
- je end_computc
- mov dx,iobase ;dx = line status register address
- add dx,5
- mov ax,_PL_comtimeout ;Start timer
- mov timer,ax
- computc_wait:
- mov ax,-1 ;Return -1 if we timed-out
- cmp timer,0
- je end_computc
- in al,dx ;Read line status register
- test al,20h ;Ready for data?
- jz computc_wait ;No, keep waiting
- mov dx,iobase ;Write character to transmit
- mov al,value ; holding register
- out dx,al
- sub ax,ax ;Return 0
- end_computc:
- ret
- computc ENDP
-
- END
-